home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
SPACE 2
/
SPACE - Library 2 - Volume 1.iso
/
program
/
561
/
prolog
/
tictac.toe
< prev
next >
Wrap
Text File
|
1991-09-08
|
4KB
|
105 lines
tictactoe :- grf_mode, grf_mse_show(0),
tag(tictactoe(human)), grf_mse_hide, txt_mode.
tictactoe(human) :- screen, play(human, [u, u, u, u, u, u, u, u, u]),
tictactoe(computer).
tictactoe(computer) :- screen, play(computer, [u, u, u, u, u, u, u, u, u]),
tictactoe(human).
play(_, Board) :- wins(o, Board), delay(500).
play(_, Board) :- wins(x, Board), delay(500).
play(_, Board) :- not member(u, Board), delay(500).
play(human, Board) :- repeat, get_move(Pos), legal(Pos, Board), !,
move(o, 0, Pos, Board, NewBoard), play(computer, NewBoard).
play(computer, Board) :- think(Board, Pos),
move(x, 0, Pos, Board, NewBoard), play(human, NewBoard).
move(Sym, N, N, [u | R], [Sym | R]) :- show(N, Sym), !.
move(Sym, N, L, [H | T], [H | NT]) :- sum(N, 1, N1), move(Sym, N1, L, T, NT).
legal(0, [u | _]) :- !.
legal(N, [_ | T]) :- sum(N1, 1, N), legal(N1, T).
get_move(Pos) :- repeat, request(X, Y), stop_button(X, Y),
less(170, X), less(X, 470), less(50, Y), less(Y, 350),
Pos is 3 * ((Y - 50) / 100) + (X - 170) / 100, !.
request(X, Y) :- repeat, grf_mse_state(0, _, _), !,
repeat, grf_mse_state(1, X, Y), !.
stop_button(X, Y) :- less(30, X), less(X, 70), less(30, Y), less(Y, 70),
tagexit(tictactoe(_)).
stop_button(_, _).
% the computer's strategy :
% try to use a winning situation
think(Board, Pos) :- insert(x, Board, Pos, NewBoard), wins(x, NewBoard).
% try to destroy the human's winning situation
think(Board, Pos) :- insert(o, Board, Pos, NewBoard), wins(o, NewBoard).
% select an empty field, but prefer center to corners to edges
think([_, _, _, _, u, _, _, _, _], 4).
think([u, _, _, _, _, _, _, _, _], 0).
think([_, _, u, _, _, _, _, _, _], 2).
think([_, _, _, _, _, _, u, _, _], 6).
think([_, _, _, _, _, _, _, _, u], 8).
think([_, u, _, _, _, _, _, _, _], 1).
think([_, _, _, u, _, _, _, _, _], 3).
think([_, _, _, _, _, u, _, _, _], 5).
think([_, _, _, _, _, _, _, u, _], 7).
insert(Sym, [u | R], 0, [Sym | R]).
insert(Sym, [H | T], N, [H | NT]) :- insert(Sym, T, N1, NT), sum(N1, 1, N).
% determining the end of a game :
wins(X, [X, X, X, _, _, _, _, _, _]).
wins(X, [_, _, _, X, X, X, _, _, _]).
wins(X, [_, _, _, _, _, _, X, X, X]).
wins(X, [X, _, _, X, _, _, X, _, _]).
wins(X, [_, X, _, _, X, _, _, X, _]).
wins(X, [_, _, X, _, _, X, _, _, X]).
wins(X, [X, _, _, _, X, _, _, _, X]).
wins(X, [_, _, X, _, X, _, X, _, _]).
delay(0).
delay(N) :- sum(N1, 1, N), bell, delay(N1).
% graphics :
screen :- grf_mse_hide, grf_f_type(2), grf_f_style(4),
grf_box(0, 0, 639, 399), grf_f_type(0), grf_rfbox(150, 30, 489, 369),
clr(50), clr(150), clr(250),
grf_f_type(2), grf_f_style(1), grf_rfbox(30, 30, 70, 70),
grf_t_effects(16),
grf_text(34, 42, 'STOP'), grf_mse_show(0).
clr(Y) :- square(170, Y), square(270, Y), square(370, Y).
show(Number, Symbol) :- prod(3, Div, Mod, Number), X is 100*Mod + 170,
Y is 100*Div + 50, grf_mse_hide, show(X, Y, Symbol), grf_mse_show(0).
show(X, Y, o) :- !, circle(X, Y).
show(X, Y, x) :- cross(X, Y).
square(X, Y) :- sum(X, 99, X1), sum(Y, 99, Y1),
grf_f_type(0), grf_bar(X, Y, X1, Y1).
circle(X, Y) :- sum(X, 50, X1), sum(Y, 50, Y1), grf_l_width(15),
grf_arc(X1, Y1, 30, 0, 3600).
cross(X, Y) :- sum(X, 20, X1), sum(Y, 20, Y1), sum(X, 80, X2), sum(Y, 80, Y2),
grf_l_width(15), grf_l_ends(2, 2),
grf_pline([X1, Y1, X2, Y2]), grf_pline([X1, Y2, X2, Y1]).
end.